perm filename IMAIN.2[EAL,HE]2 blob sn#704710 filedate 1983-03-30 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00004 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	{$NOMAIN	Interpreter: Main control loop }
C00028 00003	{ Externally defined routines from elsewhere: }
C00032 00004	(* command loop *)
C00045 ENDMK
C⊗;
{$NOMAIN	Interpreter: Main control loop }

const

  (* Constants from EDIT *)

  maxLines = 40;
  maxPPLines = 30;
  maxBpts = 25;
  maxTBpts = 20;	(* max could be exceeded by huge case stmnt *)
  listinglength = 4000;	(* Length of Listingarray *)

(* Random type declarations for OMSI/SAIL compatibility *)

type
  byte = 0..255;	(* doesn't really belong here, but... *)
  ascii = char; 
  atext = text;

{ Define all the pointer types here }

vectorp = ↑vector;
transp = ↑trans;
strngp = ↑strng;
eventp = ↑event;
framep = ↑frame;
statementp = ↑statement;
varidefp = ↑varidef;
nodep = ↑node;
pdbp = ↑pdb;
envheaderp = ↑envheader;
enventryp = ↑enventry;
environp = ↑environment;
cmoncbp = ↑cmoncb;
messagep = ↑integer;

(* This one is used whenever a pointer is needed for which the 	*)
(* definition is missing from this file; naturally, all 	*)
(* pointers use the same space 					*)

dump = ↑integer;
token = array[1..4] of integer;		{Uses same space as a token}
cursorp = array[1..4] of integer;	{Ditto, for cursorp}


(* datatype definitions *)

datatypes = (pconstype, varitype, svaltype, vectype, rottype, transtype,
	     frametype, eventtype, strngtype, labeltype, proctype, arraytype,
	     reftype, valtype, cmontype, nulltype, undeftype,
	     dimensiontype, mactype, macargtype, freevartype);

scalar = real;

u = (used,free);
vector = record case u of
	   used: (refcnt: integer; val: array [1..3] of real);
	   free: (next: vectorp);
	 end;

trans = record case u of
	   used: (refcnt: integer; val: array [1..3,1..4] of real);
	   free: (next: transp);
	end;

cstring = packed array [1..10] of ascii;
c4str = packed array [1..4] of ascii;
c5str = packed array [1..5] of ascii;
c20str = packed array [1..20] of ascii;
linestr = packed array [1..130] of ascii;

strng = record
	  next: strngp;
	  ch: cstring;
	end;

event = record
	  next: eventp;		(* all events are on one big list *)
	  count: integer;
	  waitlist: pdbp;
	end;

frame = record
	  vari: varidefp;	(* back pointer to variable name & info *)
	  calcs: nodep;		(* affixment info *)
	  case ftype: boolean of	(* frame = true, device = false *)
  true:	    (valid: integer; val, fdepr: transp; dcntr: integer; dev: framep);
  false:    (mech: integer; case sdev: boolean of
		true: (sdest: real); false: (tdest,appr,depr: transp));
		(* sdev = true for scalar devices, false for frames *)
	end;



(* statement definitions *)

stmntypes = (progtype, blocktype, coblocktype, endtype, coendtype,
		fortype, iftype, whiletype, untiltype, casetype,
		calltype, returntype,
		printtype, prompttype, pausetype, aborttype, assigntype,
		signaltype, waittype, enabletype, disabletype, cmtype,
		affixtype, unfixtype,
		movetype,jtmovetype,operatetype,opentype,closetype,centertype,
		floattype, stoptype, retrytype,
		requiretype, definetype, macrotype, commenttype, dimdeftype,
		setbasetype, wristtype, saytype, declaretype, emptytype,
		evaltype, armmagictype);
		(* more??? *)

statement = packed record
		next, last: statementp;
		stlab: varidefp;
		exprs: nodep;	(* any expressions used by this statement *)
		nlines: integer;
		bpt,bad: boolean;
		case stype: stmntypes of

    progtype:	    (pcode: statementp; errors: integer);
    blocktype,
    declaretype,
    endtype,
    coendtype:	    (bcode, bparent: statementp; blkid: dump;
			level, numvars: 0..255; variables: varidefp);
    coblocktype:    (threads: nodep; nthreads: integer; cblkid: dump);
    fortype:	    (forvar, initial, step, final: nodep; fbody: statementp);
    whiletype,
    untiltype:	    (cond: nodep; body: statementp);
    casetype:	    (index: nodep; range, ncases: integer; caselist: nodep);
    iftype:	    (icond: nodep; thn, els: statementp);
    pausetype:	    (ptime: nodep);
    prompttype,
    printtype,
    aborttype,
    saytype:	    (plist: nodep; debugLev: integer);
    returntype:	    (retval, rproc: nodep);
    evaltype,
    calltype,
    assigntype:     (what, aval: nodep);
    affixtype,
    unfixtype:	    (frame1, frame2, byvar, atexp: nodep; rigid: boolean);
    signaltype,
    waittype:	    (event: nodep);
    movetype,
    jtmovetype,
    operatetype,
    opentype,
    closetype,
    centertype,
    floattype,
    setbasetype,
    stoptype:	    (cf, clauses: nodep);
    retrytype:	    (rcode, rparent: statementp; olevel: integer);
    wristtype:	    (arm, ff, fvec, tvec: nodep; csys: boolean);
    cmtype:	    (oncond: nodep; conclusion: statementp;
			deferCm, exprCm: boolean; cdef: varidefp);
    enabletype,
    disabletype:    (cmonlab: varidefp);
    requiretype:    (rfil: boolean; rfils: strngp; rfilen: integer);
    definetype:	    (macname,mpars: varidefp; macdef: dump);
    commenttype:    (len: integer; str: strngp; cbody: statementp);
    dimdeftype:	    (dimname: varidefp; dimexpr: nodep);
    armmagictype:   (cmdnum,dev,iargs,oargs: nodep);
		end;



(* auxiliary definitions: variable, etc. *)

varidef = packed record
	    next,dnext: varidefp;
	    name: dump;
	    level: 0..255;	(* environment level *)
	    offset: 0..255;	(* environment offset *)
	    dtype: varidefp;	(* to hold the dimension info *)
	    tbits: 0..15;  (* special type bits: array = 1, proc = 2, ref = 4 & ? *)
	    dbits: 0..15;	(* for use by debugger/interpreter *)
	    case vtype: datatypes of
  arraytype:  (a: nodep);
  proctype:   (p: nodep);
  labeltype,
  cmontype:   (s: statementp);
  mactype:    (mdef: statementp);
  macargtype: (marg: dump);
  pconstype:  (c: nodep);
  dimensiontype: (dim: nodep);
	  end;



(* definition of the ubiquitous NODE record *)

nodetypes = (exprnode, leafnode, listnode, clistnode, colistnode, forvalnode,
		deprnode, viaptnode, apprnode, destnode, byptnode, durnode,
		sfacnode, wobblenode, swtnode, nullingnode, wristnode, cwnode,
		arrivalnode, departingnode,
		ffnode, forcenode, stiffnode, gathernode, cmonnode, errornode,
		calcnode, arraydefnode, bnddefnode, bndvalnode,
		waitlistnode, procdefnode, tlistnode, dimnode, commentnode,
		linearnode, elbownode, shouldernode, flipnode, wrtnode,
		loadnode,velocitynode);

exprtypes =  (	svalop,					(* scalar operators *)
		sltop, sleop, seqop, sgeop, sgtop, sneop,	(* relations *)
		notop, orop, xorop, andop, eqvop,		(* logical *)
		saddop, ssubop, smulop, sdivop, snegop, sabsop, (* scalar ops *)
		sexpop, maxop, minop, intop, idivop, modop,
		sqrtop, logop, expop, timeop,			(* functions *)
		sinop, cosop, tanop, asinop, acosop, atan2op,	(* trig *)
		vdotop, vmagnop, tmagnop,
		vecop,					(* vector operators *)
		vmakeop, unitvop, vaddop, vsubop, crossvop, vnegop,
		svmulop, vsmulop, vsdivop, tvmulop, wrtop,
		tposop, taxisop,
		transop,				(* trans operators *)
		tmakeop, torientop, ttmulop, tvaddop, tvsubop, tinvrtop,
		vsaxwrop, constrop, ftofop, deproachop, fmakeop, vmkfrcop,
		ioop,					(* i/o operators *)
		queryop, inscalarop,
		specop,					(* special operators *)
		arefop, callop, grinchop, macroop, vmop, adcop, dacop, jointop,
		badop,
		addop, subop, negop, mulop, divop, absop); (* for parsing *)

leaftypes = pconstype..strngtype;

reltypes = sltop..sgtop;
forcetypes = (force,absforce,torque,abstorque,angvelocity);

node = record
	next: nodep;
	case ntype: nodetypes of
    exprnode:	(op: exprtypes; arg1, arg2, arg3: nodep; elength: integer);
    leafnode:	(case ltype: leaftypes of
	varitype:  (vari: varidefp; vid: dump);
	pconstype: (cname: varidefp; pcval: nodep);
	svaltype:  (s: scalar; wid: integer);
	vectype:   (v: vectorp);
	transtype: (t: transp);
	strngtype: (length: integer; str: strngp) ); (* also used by commentnodes *)
    listnode:	(lval: nodep);
    clistnode:	(cval: integer; stmnt: statementp; clast: nodep);
    colistnode:	(prev: nodep; cstmnt: statementp);
    forvalnode:	(fvar: enventryp; fstep: scalar);
    arrivalnode:(evar: varidefp);
    arraydefnode: (numdims: 1..10; bounds: nodep; combnds: boolean);
    bnddefnode:	(lower, upper: nodep);
    bndvalnode:	(lb, ub, mult: integer);
    waitlistnode: (who: pdbp; when: integer);
    procdefnode:(ptype: datatypes; level: 0..255;
		    pname, paramlist: varidefp; body: statementp);
	end;



(* process descriptor blocks & environment record definitions *)

queuetypes = (nullqueue,nowrunning,runqueue,inputqueue,eventqueue,sleepqueue,
		forcewait,devicewait,joinwait,proccall);

pdb = packed record
	nextpdb,next: pdbp;	(* for list of all/active pdb's *)
	level: 0..255;		(* lexical level *)
	mode: 0..255;		(* expression/statement/sub-statement *)
	priority: 0..255;	(* probably never greater than 3? *)
	status: queuetypes;	(* what are we doing *)
	env: envheaderp;
	spc: statementp;	(* current statement *)
	epc: nodep;		(* current expression (if any) *)
	sp: nodep;		(* intermediate value stack *)
	cm: cmoncbp;		(* if we're a cmon point to our definition *)
	mech: framep;		(* current device being used *)
	linenum: integer;	(* used by editor/debugger *)
	 case procp: boolean of	(* true if we're a procedure *)
true:  (opdb: pdbp;		(* pdb to restore when procedure exits *)
	pdef: nodep);		(* procedure definition node *)
false: (evt: eventp;		(* event to signal when process goes away *)
	sdef: statementp);	(* first statement where process was defined *)
      end;


envheader = packed record
	      parent: envheaderp;
	      env: array [0..4] of environp;
	      varcnt: 0..255;		(* # of variables in use ??? *)
		case procp: boolean of  (* true if we're a procedure *)
	true: (proc: nodep);
	false:(block: statementp);
	    end;

enventry = record
	    case etype: datatypes of
  strngtype: (length: integer; str: strngp);
  proctype:  (p: nodep; penv: envheaderp);
	   end;


environment = record
		next: environp;
		vals: array [0..9] of enventryp;
	      end;


cmoncb = record
	   running, enabled: boolean;		(* cmon's status *)
	   cmon: statementp;
	   pdb: pdbp;
	   evt: eventp;
	   fbits: integer;			(* bits for force sensing *)
	   oldcmon: cmoncbp;			(* for debugger *)
	 end;



listingarray = packed array [0..listinglength] of ascii;


(* global variables *)

var
	(* from EDIT *)
    listing: listingarray;  (* first 150 chars are used by expression editor *)
			    (* next 40 by header & trailer lines *)
{*} cursorStack: array [1..15] of cursorp;	{These are BIG records! }
(*  lbuf: array [1..160] of ascii;
    ppBuf: array [1..100] of ascii; *)
    dum1: array[1..260] of ascii;
    lines: array [1..maxLines] of dump; 
    ppLines: array [1..maxPPLines] of dump;	
(*  marks: array [1..20] of integer;
    reswords: array [0..26] of reswordp;
    idents: array [0..26] of identp;
    macrostack: array [1..10] of tokenp;
    curmacstack: array [1..10] of varidefp;
    screenheight,dispHeight: integer;
    ppBufp,oppBufp,ppOffset,ppSize,nmarks: integer;
    lbufp,cursor,ocur,cursorLine,fieldnum,lineNum,findLine,pcLine: integer;
    firstDline,topDline,botDline,firstLine,lastLine,curLine: integer;
    freeLines,oldLines: linerecp;
    sysVars: varidefp;
    dProg: statementp;
    curBlock, newDeclarations, findStmnt: statementp;
    macrodepth: integer;
    filedepth, errCount, sCursor: integer;
    curChar, maxChar, curFLine, curPage: integer;
    nodim, distancedim, timedim, angledim,
      forcedim, torquedim, veldim, angveldim: varidefp;
    fvstiffdim, mvstiffdim: nodep;
    pnode: nodep;
*)  dum2: array[1..141] of dump;
(*  smartTerminal: boolean; 
    setUp,setExpr,setCursor,dontPrint,outFilep,collect,fParse,sParse,
      eofError,endOfLine,backup,expandmacros,flushcomments,checkDims,
      shownLine: boolean;
*)  dum3: array[1..16] of boolean;
    curtoken: token;
    file1,file2,file3,file4,file5,outFile: atext;

    bpts: array [1..maxBpts] of statementp;	(* debugging crap *)
    tbpts: array [1..maxTBpts] of statementp;
    debugPdbs: array [0..10] of pdbp;
(*  nbpts,ntbpts,debugLevel: integer;
    eCurInt: pdbp;
    STLevel: integer;
*)  dum4: array[1..5] of integer;
    singleThreadMode,tSingleThreadMode: boolean;

	(* from INTERP *)
    inputLine: array [1..20] of ascii;
    talk: text;			(* for using the speech synthesizer *)
    curInt, activeInts, readQueue, allPdbs: pdbp;
    sysEnv: envheaderp;
    clkQueue: nodep;
    allEvents: eventp;
    etime: integer;		(* used by eval *)
    curtime: integer; (* who knows where this will get updated - an ast? *)
    stime: integer;		(* used for clock queue on 10 *)
    msg: messagep;		(* for AL-ARM interaction *)
    inputp: integer;		(* current offset into inputLine array above *)
    resched, running, escapeI, iSingleThreadMode: boolean;
    msgp: boolean;		(* flag set if any messages pending *)
    inputReady: boolean;

(* various constant pointers *)
    xhat,yhat,zhat,nilvect: vectorp;
    niltrans: transp;
    gpark, rpark: transp;		(* arm park positions *)

(* various device & variable pointers *)
    speedfactor: enventryp;
    garm: framep;

	(* from ALLOC *)
(*  freeVectors: vectorp;
    freeTrans: transp;
    freeNodes: nodep;
    free4: s4p;
    free8: s8p;
    free10: statementp;
    free11: s11p;
    cv,ct,cn,c4,c8,c10,c11: integer;	
    ccv,cct,ccn,cc4,cc8,cc10,cc11: integer;	
*)  dum5: array[1..21] of integer;

{ Externally defined routines from elsewhere: }

	(* From ALLOC *)
procedure relNode(n: nodep);					external;

	(* From RSXMSG *)
function GetArm: boolean;                                    	external;

	(* From IAUX1A *)
function pop: nodep;						external;

	(* From IAUX1B *)
procedure getTime(var curTime: integer);			external;
procedure addPdb(var plist: pdbp; pn: pdbp);			external;
procedure msgDispatch;						external;

	(* From IEXPR *)
procedure evalExp;						external;

	(* From IOV1 *)
procedure doProg;						external;
procedure doBlock;						external;
procedure doCoblock;						external;
procedure doEnd;						external;
procedure doFor;						external;
procedure doIf;							external;
procedure doWhile;						external;
procedure doUntil;						external;

	(* From IOV2 *)
procedure doCase;						external;
procedure doCall;						external;
procedure doReturn;						external;
procedure doAssign;						external;
procedure doPrompt;						external;
procedure doSignal;						external;
procedure doWait;						external;

	(* From IOV3 *)
procedure doEnable;						external;
procedure doDisable;						external;
procedure doAffix;						external;
procedure doUnfix;						external;

	(* From IOV4 *)
procedure doPrint;						external;
procedure doPause;						external;
procedure doAbort;						external;
procedure doSetbase;						external;
procedure doWrist;						external;
procedure doRetry;						external;

	(* From IOV5 *)
procedure doSay;						external;
procedure doFloat;						external;

	(* From IMOVE1 *)
procedure doMove;						external;

	(* From IMOVE2 *)
procedure doCmon;						external;
procedure doOperate;						external;
procedure doOpen; (* & doClose *)				external;
procedure doCenter;						external;
procedure doStop;						external;
procedure doArmmagic;						external;

	(* Display-related Routines *)
procedure ppLine; 						external;
procedure ppOutNow; 						external;
procedure ppChar(ch: ascii); 					external;
procedure pp5(ch: c5str; length: integer); 			external;
procedure pp10(ch: cstring; length: integer); 			external;
procedure pp10L(ch: cstring; length: integer);			external;
procedure pp20(ch: c20str; length: integer); 			external;
procedure pp20L(ch: c20str; length: integer); 			external;
procedure ppInt(i: integer); 					external;
procedure ppDelChar; 						external;
function anyChar(var ch: ascii): boolean;			external;	

	(* From RSXRUT *)
procedure markTime(when: integer; var curTime,stime: integer);	external;

(* command loop *)

procedure interp(dLev: integer); external;
procedure interp;
 var p,pp: pdbp; n: nodep; b,breakNow: boolean; 
     ch: ascii; 
     minPriority, ti: integer;
 begin
(* debugLevel := dLev;		(* already set by edit *)
 minPriority := 10 * debugLevel;
 if curInt <> nil then curInt↑.status := nowrunning;
 running := true;		(* Means we're now running some process *)
 resched := false;		(* Don't reschedule until we have to *)
 breakNow := false;		
 escapeI := false;
 inputp := 0;
 inputReady := false;
 msgp := False;			(* Reset "messages-pending" flag *)
 stime := 0;			(* No time-ticks waiting yet *)
 curTime := 0;			(* Zero current time *)
 if readQueue <> nil then
  if readQueue↑.priority >= minPriority then	(* must be at current level *)
   with readQueue↑ do
    begin			(* remind user we're waiting for input *)
    b := true;
    if epc <> nil then
      begin
      b := false;
      if epc↑.op = queryop then pp20L('Type Y or N:        ',13)
       else if epc↑.op = inscalarop then pp20L('Scalar please:      ',15)
       else b := true;
      end;
    if b then
      begin
      b := false;
      if (spc↑.stype = prompttype) or (spc↑.stype = waittype) then
	pp20L('Type P to proceed:  ',19)
       else if (movetype <= spc↑.stype) and (spc↑.stype <= centertype) then
	begin
	pp20L('"P" to proceed, "R" ',20); pp20('to retry the motion ',19);
	if (spc↑.stype <> operatetype) and (spc↑.stype <> centertype) then
	  begin pp20(', "F" to move direct',20);
		pp20('ly to destination   ',17) end;
	pp20L('  or B to break to d',20); pp10('ebugger:  ',9);
	end
       else b := true;
      end;
    if not b then ppOutNow;
(* *** else ??? flush readQueue ??? *** *)
    end;

 while running do
  begin

  if msgp then			(* any messages pending? *)
    repeat			(* yup - go read them *)
     msgp := false;		(* reset flag *)
     b := getArm;		(* read next message *)
     if b then msgDispatch	(* if we actually got one then deal with it *)
    until not b;		(* keep going til no more messages to read *)

  if stime <> 0 then		(* Time to wake up sleeping processes *)
    begin
    stime := 0;		(* *** maybe subtract one instead??? *** *)
    ti := curTime;		(* remember old time: last time something got scheduled *)
    getTime(curTime);		(* and get current time; store in curTime *)
    ti := -((curTime - ti) MOD 18000); (* time since last request was scheduled *)
    repeat			(* schedule all now active processes *)
     n := clkQueue;		(* get waitlist node *)
     p := n↑.who;
     while p <> nil do		(* add waiting processes to activeInts list *)
      begin
      pp := p↑.next;		(* remember where we are in list *)
      addPdb(activeInts,p);
      p := pp;
      end;
     clkQueue := n↑.next;	(* check if time for next to be awakened *)
     relNode(n);
     if clkQueue = nil then ti := 0
      else
       ti := clkQueue↑.when + ti  (* when we really want to schedule request *)
    until ti >= 0;
    if clkQueue <> nil then
      markTime(ti,curTime,stime);	(* schedule next one to be run *)
    if curInt = nil then resched := true
     else if activeInts↑.priority > curInt↑.priority then resched := true;
    end;

  if resched then			(* schedule highest priority process *)
    begin
    resched := false;
    if curInt <> nil then
      begin
      curInt↑.status := runqueue; 
      addPdb(activeInts,curInt);
      end;
    curInt := activeInts;	(* now swap in highest priority process *)
    if activeInts <> nil then
      begin
      activeInts := activeInts↑.next;
      curInt↑.next := nil;
      curInt↑.status := nowrunning;
      with curInt↑ do
       breakNow := (mode = 0) and (spc↑.bpt or spc↑.bad);
      end;
    end;

  if readQueue <> nil then  (* is some process waiting for terminal input? *)
   if readQueue↑.priority >= minPriority then	(* must be at current level *)
    while anyChar(ch) and (not inputReady) do
     begin
     if ch = chr(15B) then
       begin				(* process the line now *)
       ppLine;					(* echo it *)
       inputReady := true;
       if inputp = 0 then inputLine[1] := ' ';	(* for empty lines *)
       if curInt <> nil then
	 begin
	 curInt↑.status := runqueue; 
	 curInt↑.next := activeInts;
	 activeInts := curInt;
	 resched := curInt↑.priority > readQueue↑.priority; (* for next time *)
	 end;
       curInt := readQueue;	(* swap input process in now *)
       curInt↑.status := nowrunning;
       readQueue := curInt↑.next;  (* might be a lower level joker in queue *)
       curInt↑.next := nil;
       breakNow := false;
       end
      else if (ord(ch) = 10B) or (ord(ch) = 177B) then	(* backspace/delete *)
       begin
       if inputp > 0 then
	 begin				(* something to delete *)
	 inputLine[inputp] := ' ';
	 inputp := inputp - 1;
	 ppDelChar;			(* erase last character *)
	 end
       end
      else if ch <> chr(12B) then	(* ignore linefeeds *)
       begin
       inputp := inputp + 1;	(* *** should check for array overflow *** *)
       inputLine[inputp] := ch;
       ppChar(ch); ppOutNow;		(* echo it *)
       end
     end;

  if (curInt <> nil) and (not breakNow) then	(* something to do now *)
   with curInt↑ do
    if priority >= minPriority then	(* must be at current level *)
     if epc <> nil then evalExp	(* continue evaluating current expression *)
      else if curInt↑.mode = 0 then
       begin	(* evaluate any expressions needed by current statement *)
       epc := spc↑.exprs;
       mode := 1;
       if spc↑.stype = untiltype then epc := nil  (* evaluate condition later *)
	else if spc↑.stype = cmtype then	(* treat enabling a cmon specially *)
	 if cm = nil then epc := nil
	  else if cm↑.cmon <> spc then epc := nil
	  else mode := 2;			(* we're doing the ON cond *)
       end
      else case spc↑.stype of	(* interpret the current statement *)
progtype:	doProg;
blocktype:	doBlock;
coblocktype:	doCoblock;
coendtype,
endtype:	doEnd;
fortype:	doFor;
iftype:		doIf;
whiletype:	doWhile;
untiltype:	doUntil;
casetype:	doCase;
calltype:	doCall;
returntype:	doReturn;
printtype:	doPrint;
prompttype:	doPrompt;
pausetype:	doPause;
aborttype:	doAbort;
saytype:	doSay;
assigntype:	doAssign;
signaltype:	doSignal;
waittype:	doWait;
enabletype:	doEnable;
disabletype:	doDisable;
cmtype:		doCmon;
affixtype:	doAffix;
unfixtype:	doUnfix;
movetype,
jtmovetype:	doMove;
operatetype:	doOperate;
opentype,
closetype:	doOpen;		(* someday close may be different ... *)
centertype:	doCenter;
stoptype:	doStop;
floattype:	doFloat;
retrytype:	doRetry;
setbasetype:	doSetbase;
wristtype:	doWrist;
armmagictype:	doArmmagic;
evaltype,
commenttype,
emptytype,
requiretype,
definetype,
declaretype,
dimdeftype:	begin
		if spc↑.stype = evaltype then
		  spc↑.aval := pop;		(* get value for EDIT *)
		mode := 0;
		spc := spc↑.next;		(* move on *)
		end;
(* more??? *)
otherwise {do nothing - maybe complain?? };
    end;

  if (curInt <> nil) and running then	(* check if we've hit a breakpoint *)
    with curInt↑ do
     if priority >= minPriority then	(* must be at current level *)
       running := not((mode = 0) and (spc↑.bpt or spc↑.bad));

  if escapeI then
    begin
    b := running;
    if curInt = nil then running := false
     else with curInt↑ do
      if priority < minPriority then running := false
       else if curInt↑.mode = 0 then	(* ready to start some real stmnt? *)
	if (spc↑.stype <> endtype) and (spc↑.stype <> coendtype) then
	  running := false;
    if b and not running then pp20L('Control-C Interrupt ',19);
    end;

  end;	(* repeat til done running *)

(* finish up - leave things in a clean state *)

 end;